TableReadContent Subroutine

private subroutine TableReadContent(lines, tab)

read the content of the table. Arguments: lines collection of strings that contain table information tab table to update

Arguments

Type IntentOptional Attributes Name
character(len=LINELENGTH), intent(in), POINTER :: lines(:)
type(Table), intent(out) :: tab

Variables

Type Visibility Attributes Name Initial
character(len=LINELENGTH), public :: before
integer(kind=long), public :: i
integer(kind=long), public :: j
integer(kind=long), public :: k
character(len=LINELENGTH), public :: string

Source Code

SUBROUTINE TableReadContent &
  ( lines, tab )
  
! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringSplit, StringToUpper

IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = LINELENGTH), INTENT (IN), POINTER :: lines (:)

! Array arguments with intent (out):
TYPE (Table), INTENT (OUT) :: tab
! Local scalars:
CHARACTER (LEN = LINELENGTH)  :: string
CHARACTER (LEN = LINELENGTH)  :: before
INTEGER (KIND = long) :: i, j, k

! Local Arrays:

!------------end of declaration------------------------------------------------

string = ''
i = 0

! scan table to find lines that have not a keyword.
DO k = 1, SIZE (lines)
  string =  lines (k)
  !CALL StringSplit ( ':', string, before)
  
  IF ( StringToUpper ( string(1:6)) == "TITLE:"        .OR. &
       StringToUpper ( string(1:3)) == "ID:"           .OR. &
       StringToUpper ( string(1:6)) == "UNITS:"        .OR. &
       StringToUpper ( string(1:8)) == "COLUMNS:"      .OR. &
       StringToUpper ( string(1:11)) == "TABLE START" .OR. &
       StringToUpper ( string(1:9)) == "TABLE END") THEN 
    ! this is a line with a keyword not a row of table
  ELSE
    !remove inline comments
    CALL StringSplit ( '#', string, before) !remove inline comments
    string = before
    !increment row
    i = i + 1
    READ(string,*) ( tab % col (j) % row (i), j = 1, tab % noCols )
  END IF
END DO

END SUBROUTINE TableReadContent